home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
prolog
/
brklyprl.lha
/
Comp
/
valvar.pl
< prev
next >
Wrap
Text File
|
1989-04-14
|
3KB
|
103 lines
/* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
/* Copyright Herve' Touati, Aquarius Project, UC Berkeley */
% Value-variable annotation:
% Assumes that initializations of variables
% that needed it have been added to the code.
% Assumes that code still contains disjunction structure.
% Pass 1: First occurrences of all variables are
% marked 'variable'. All variables occurring
% first in a 'put' are marked unsafe. Later,
% 'excess' will only allow permanents to keep
% the unsafe annotation.
% Pass 2: Do a reverse pass. First encounters of
% unsafe variables are marked 'unsafe_value',
% unless they are already marked 'variable'.
% All other encounters with variables are marked
% 'value'.
% Must be done before temporary variable allocation and
% after calculation of permanent variables.
% Variables encountered so far are kept in the set SoFar
% in both passes. This set is passed in parallel across
% disjunctions, and the different SoFar's are united upon
% exiting disjunctions.
% Top level:
valvar(PartObj, HeadVars) :-
valvar1(PartObj, [], PossUnSafe, [], _), !,
diffv(PossUnSafe, HeadVars, UnSafe),
valvar2(PartObj, UnSafe, [], _), !.
% Pass 1:
valvar1(V, UnSafe, UnSafe, SF, SF) :- (var(V);V=[]).
valvar1([(A;B)|RestCode], InUS, OutUS, SoFar, OutSF) :-
disvalvar1((A;B), InUS, US1, SoFar, NewSF),
valvar1(RestCode, US1, OutUS, NewSF, OutSF).
valvar1([G-L|RestCode], InUS, OutUS, SoFar, OutSF) :-
valvar1(G, InUS, US1, SoFar, NewSF),
valvar1(RestCode, US1, OutUS, NewSF, OutSF).
valvar1([I|RestInstr], InUS, OutUS, SoFar, OutSF) :-
type_arg(I, T, X), !,
(notin(X, SoFar) , T=variable; true),
new_us(I, X, SoFar, InUS, US1),
unionv([X], SoFar, NewSF),
valvar1(RestInstr, US1, OutUS, NewSF, OutSF).
valvar1([_|RestInstr], InUS, OutUS, SoFar, OutSF) :-
valvar1(RestInstr, InUS, OutUS, SoFar, OutSF).
new_us(I, X, SoFar, InUS, US1) :-
I=put(_,_,_), notin(X, SoFar), !,
unionv([X], InUS, US1).
new_us(I, X, SoFar, InUS, InUS).
disvalvar1((A;B), InUS, OutUS, SoFar, OutSF) :-
valvar1(A, InUS, US1, SoFar, Out1),
disvalvar1(B, US1, OutUS, SoFar, Out2),
unionv(Out1, Out2, OutSF).
disvalvar1(B, InUS, OutUS, SoFar, OutSF) :-
valvar1(B, InUS, OutUS, SoFar, OutSF).
% Pass 2:
valvar2(V, _, SF, SF) :- (var(V); V=[]).
valvar2([(A;B)|RestCode], UnSafe, SoFar, OutSF) :-
valvar2(RestCode, UnSafe, SoFar, NewSF),
disvalvar2((A;B), UnSafe, NewSF, OutSF).
valvar2([G-L|RestCode], UnSafe, SoFar, OutSF) :-
valvar2(RestCode, UnSafe, SoFar, NewSF),
valvar2(G, UnSafe, NewSF, OutSF).
valvar2([I|RestInstr], UnSafe, SoFar, OutSF) :-
type_arg(I, T, X), !,
valvar2(RestInstr, UnSafe, SoFar, NewSF),
choose_annotation(X, UnSafe, NewSF, T),
unionv([X], NewSF, OutSF).
valvar2([_|RestInstr], UnSafe, SoFar, OutSF) :-
valvar2(RestInstr, UnSafe, SoFar, OutSF).
choose_annotation(X, UnSafe, NewSF, T) :-
in(X, UnSafe), notin(X, NewSF), !,
make_unsafe_value(T).
choose_annotation(X, UnSafe, NewSF, T) :-
make_value(T).
disvalvar2((A;B), UnSafe, SoFar, OutSF) :-
valvar2(A, UnSafe, SoFar, Out1),
disvalvar2(B, UnSafe, SoFar, Out2),
unionv(Out1, Out2, OutSF).
disvalvar2(B, UnSafe, SoFar, OutSF) :-
valvar2(B, UnSafe, SoFar, OutSF).
% Make unsafe_value if possible
make_unsafe_value(unsafe_value) :- !.
make_unsafe_value(_) :- !.
% Make value if possible
make_value(value) :- !.
make_value(_) :- !.